home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Shareware Grab Bag
/
Shareware Grab Bag.iso
/
090
/
cmln1285.arc
/
TWS.LST
< prev
next >
Wrap
File List
|
1986-02-27
|
20KB
|
602 lines
C:\TWS\TEST>pg prolog6
C:\TWS\TEST>echo off
MetaWare TWS Skeleton. 30-Sep-85 19:29:03 prolog6.pg Page 1
Scanner Grammar_lexicon(15-May-85 07:35:58)
Parser PSG_syntax(23-Feb-85 23:34:47)
LINE # |----+----1----+----2----+----3----+----4----+----5----+----6----+----7-
1 |parser Start:
2 |
3 |Start -> Prolog
4 |;
5 |Prolog -> Prolog Clause
6 | -> Clause
7 |;
8 |Clause -> Goals '.'
9 | -> Goals ':-' Goals '.'
10 |;
11 |Goals -> Goals ',' Goal
12 | -> Goal
13 |;
14 |Goal -> Predicate '(' Components ')'
15 |;
16 |Components -> Components ',' Component
17 | -> Component
18 |;
19 |Component -> Functor '(' Components ')'
20 | -> '<VARIABLE>'
21 | -> Constant
22 | -> List
23 |;
24 |Constant -> '<NUMBER>'
25 | -> '<ATOM>'
26 |;
27 |Functor -> '<ATOM>'
28 |;
29 |Predicate -> '<ATOM>'
30 |;
31 |List -> '[' ']'
32 | -> '[' Head ']'
33 | -> '[' Head '|' Tail ']'
34 |;
35 |Head -> Components
36 |;
37 |Tail -> List
38 |;
39 |end Start
40 |do xref print_dpda
41 |
No user errors No warnings 286K of memory unused.
End of processing, 30-Sep-85 19:29:07 prolog6.pg
MetaWare LALR(1) Grammar Analyzer. Today is 30-Sep-85 19:29:13
Removing the unit production for Predicate
Removing the unit production for Functor
Removing the unit production for Head
Removing the unit production for Tail
Back substituting all productions for Constant
-- Grammar flattened (regular expressions removed).
Grammar: 14 terminals, 9 nonterminals, and 18 productions.
42 is the total right part length.
V O C A B U L A R Y C R O S S - R E F E R E N C E
===================================================
'(' 8 11
')' 8 11
',' 6 9
'.' 4 5
':-' 5
'<ATOM>' 8 11 13
'<END_OF_FILE>' 0
'<ILLEGAL_CHARACTER>'
'<ILLEGAL_SYMBOL>'
'<NUMBER>' 14
'<VARIABLE>' 12
'[' 16 17 18
']' 16 17 18
'|' 18
<system_goal_symbol> 0*
Clause 2 3 4* 5*
Component 9 10 11* 12* 13* 14* 15*
Components 8 9 11 17 18 9* 10*
Goal 6 7 8*
Goals 4 5 5 6 6* 7*
List 15 18 16* 17* 18*
Prolog 1 2 2* 3*
Start 0 1*
-- Grammar processing complete.
-- LR(0) parser: 36 states
38 terminal transitions
23 nonterminal transitions
29 nuclei items
-- Look-ahead sets:
Relation Examined/Edges SCCs Nodes
------------------------------------------
Reads 0/ 0 0 0
Follow 8/ 8 0 0
2 final items in 2 states needed SLR(1) look-ahead sets.
0 final items in 0 states needed LALR(1) look-ahead sets.
0 look-ahead sets were used in total.
8 set unions for computing SLR(1) look-ahead sets.
-- The grammar is LALR(1); in fact, it is SLR(1).
DPDA:
State 19, accessed by
Terminal transitions Nonterminal transitions
'<ATOM>' -> 23 Start -> 20
Prolog -> 21
Clause -> 3
Goals -> 22
Goal -> 7
State 20, accessed by Start
Terminal transitions Nonterminal transitions
'<END_OF_FILE>' -> 0
State 21, accessed by Prolog
Terminal transitions Nonterminal transitions
'<ATOM>' -> 23 Clause -> 2
Goals -> 22
Goal -> 7
Look-ahead transitions
{ '<END_OF_FILE>' } -> 1 Start -> Prolog
State 22, accessed by Goals
Terminal transitions Nonterminal transitions
':-' -> 24
',' -> 25
'.' -> 4
State 23, accessed by '<ATOM>'
Terminal transitions Nonterminal transitions
'(' -> 26
State 24, accessed by Goals ':-'
Terminal transitions Nonterminal transitions
'<ATOM>' -> 23 Goals -> 27
Goal -> 7
State 25, accessed by Goals ','
Terminal transitions Nonterminal transitions
'<ATOM>' -> 23 Goal -> 6
State 26, accessed by '<ATOM>' '('
Terminal transitions Nonterminal transitions
'<ATOM>' -> 29 Components -> 28
'<VARIABLE>' -> 12 Component -> 10
'<NUMBER>' -> 14 List -> 15
'[' -> 30
State 27, accessed by Goals ':-' Goals
Terminal transitions Nonterminal transitions
',' -> 25
'.' -> 5
State 28, accessed by '<ATOM>' '(' Components
Terminal transitions Nonterminal transitions
',' -> 31
')' -> 8
State 29, accessed by '<ATOM>' '(' '<ATOM>'
Terminal transitions Nonterminal transitions
'(' -> 32
Look-ahead transitions
{ ')' ',' ']' '|' } -> 13 Component ->
'<ATOM>'
State 30, accessed by '<ATOM>' '(' '['
Terminal transitions Nonterminal transitions
']' -> 16 Components -> 33
'<ATOM>' -> 29 Component -> 10
'<VARIABLE>' -> 12 List -> 15
'<NUMBER>' -> 14
'[' -> 30
State 31, accessed by '<ATOM>' '(' Components ','
Terminal transitions Nonterminal transitions
'<ATOM>' -> 29 Component -> 9
'<VARIABLE>' -> 12 List -> 15
'<NUMBER>' -> 14
'[' -> 30
State 32, accessed by '<ATOM>' '(' '<ATOM>' '('
Terminal transitions Nonterminal transitions
'<ATOM>' -> 29 Components -> 34
'<VARIABLE>' -> 12 Component -> 10
'<NUMBER>' -> 14 List -> 15
'[' -> 30
State 33, accessed by '<ATOM>' '(' '[' Components
Terminal transitions Nonterminal transitions
',' -> 31
'|' -> 35
']' -> 17
State 34, accessed by '<ATOM>' '(' '<ATOM>' '(' Components
Terminal transitions Nonterminal transitions
',' -> 31
')' -> 11
State 35, accessed by '<ATOM>' '(' '[' Components '|'
Terminal transitions Nonterminal transitions
'[' -> 30 List -> 36
State 36, accessed by '<ATOM>' '(' '[' Components '|' List
Terminal transitions Nonterminal transitions
']' -> 18
-- Table packing:
0 multiply inconsistent states.
16 nonterminal transitions saved by default.
38 terminal entries in the comb.
29 teeth in terminal portion.
27 are non-empty.
16 nonterminal entries in the comb.
48 teeth in entire comb.
43 are non-empty.
5 of 9 SLR(1) look-ahead sets were distinct.
Total (uncompressed) table size is
344 bytes of parse tables
+ 200 bytes of vocabulary
+ 84 bytes of error recovery info
= 628 total.
Parse tables written to disk.
No user errors.
End of processing, 30-Sep-85 19:29:21
C:\TWS\TEST>sg prolog3
C:\TWS\TEST>echo off
MetaWare TWS Skeleton. 30-Sep-85 18:56:29 prolog3.sg Page 1
Scanner Grammar_lexicon(15-May-85 07:35:58)
Parser Lex_syntax(26-Jun-85 16:45:43)
LINE # |----+----1----+----2----+----3----+----4----+----5----+----6----+----7-
1 |#-set lower_case
2 |
3 |scanner Prolog_text:
4 |
5 |Prolog_text -> (Pseudo | Separator)*;
6 | Pseudo -> Variable | String | Symbol | Number;
7 | Separator-> Punctuator | Spaces | Eol;
8 |
9 |Variable -> Varhead (Letter | Digit)* => '<VARIABLE>';
10 | Varhead -> (Uppercase | Underscore);
11 | Letter -> Uppercase | Lowercase;
12 | Uppercase-> 'A' .. 'Z';
13 | Lowercase-> 'a' .. 'z';
14 | Digit -> '0' .. '9';
15 | Underscore-> '_';
16 |
17 |String -> (Quote Chars Quote)+ => '<ATOM>';
18 | Quote -> '''';
19 | Chars -> (Any - Quote)*;
20 |
21 |Symbol -> Lowercase (Letter | Digit)* => '<ATOM>' ;
22 |
23 |Number -> '-'? Digit+ => '<NUMBER>';
24 |
25 |Punctuator -> '(' | ')' | ',' | '[' | ']'
26 | | '.' | '|' | ':' '-' => '<AS_IS>';
27 |
28 |Spaces -> Space+ => '<DELETE>';
29 |Space -> ' ' | Tab;
30 | Tab -> 'ht';
31 |
32 |
33 |end Prolog_text
34 |
No user errors No warnings 287K of memory unused.
End of processing, 30-Sep-85 18:56:33 prolog3.sg
MetaWare Scanner Generator. Today is 30-Sep-85 18:56:39
-- Grammar constraints checked.
-- FSM generated: 13 states.
564 transitions.
1 nuclei in largest nucleus bucket.
12 items in all the nuclei.
-- Code generation:
150 entries in the comb.
130 teeth in the comb.
75 are non-empty.
74 words of s-code generated.
Total table size is
584 bytes of scan tables
+ 143 bytes of vocabulary/tracing info
= 727 total.
Scan tables written to disk.
End of processing, 30-Sep-85 18:56:46
C:\TWS\TEST>pg psg2
C:\TWS\TEST>echo off
MetaWare TWS Skeleton. 30-Sep-85 18:56:58 psg2.pg Page 1
Scanner Grammar_lexicon(15-May-85 07:35:58)
Parser PSG_syntax(23-Feb-85 23:34:47)
LINE # |----+----1----+----2----+----3----+----4----+----5----+----6----+----7-
1 |parser PSG:
2 |
3 |PSG -> Program;
4 |Program -> ProgHead ProgParms ';' Pblk Pblock '.';
5 |
6 |ProgHead -> 'PROGRAM' '<IDENTIFIER>';
7 |ProgParms -> ;
8 |
9 |Pblock -> LBList TYPList VRList PList Pbegin StmtList 'END';
10 |Pbegin -> 'BEGIN';
11 |
12 |Block -> 'BEGIN' StmtList 'END';
13 |
14 |LBList -> 'LABEL' LabList ';'
15 | -> ;
16 |LabList -> LabList ',' '<INTEGER>'
17 | -> '<INTEGER>';
18 |
19 |VRList -> Var VList ';'
20 | -> ;
21 |Var -> 'VAR';
22 |VList -> VList ';' VarItem
23 | -> VarItem;
24 |VarItem -> IdentList ':' Type;
25 |IdentList -> IdentList ',' '<IDENTIFIER>'
26 | -> '<IDENTIFIER>';
27 |
28 |TYPList -> 'TYPE' TList ';'
29 | -> ;
30 |TList -> TList ';' TypItem
31 | -> TypItem;
32 |TypItem -> '<IDENTIFIER>' '=' Type;
33 |
34 |Type -> SimpType
35 | -> 'ARRAY' '[' Sint '..' Sint ']' 'OF' Type
36 | -> 'RECORD' FieldList 'END';
37 |
38 |SimpType -> '<IDENTIFIER>';
39 |
40 |
41 |FieldList -> IdentList ':' Type
42 | -> IdentList ':' Type ';' FieldList
43 | -> 'CASE' SimpType 'OF' CaseList;
44 |
45 |
46 |CaseList -> CaseItem ';' CaseList
47 | -> CaseItem;
48 |CaseItem -> ConstList ':' '(' FieldList ')';
49 |
50 |PList -> PList PFDecl
51 | -> ;
52 |PFDecl -> ProcDecl
53 | -> FuncDecl;
54 |ProcDecl -> ProcHead Parms ';' 'FORWARD' ';'
55 | -> ProcHead Parms ';' Pblk Pblock ';';
MetaWare TWS Skeleton. 30-Sep-85 18:56:58 psg2.pg Page 2
LINE # |----+----1----+----2----+----3----+----4----+----5----+----6----+----7-
56 |ProcHead -> 'PROCEDURE' '<IDENTIFIER>';
57 |FuncDecl -> FuncHead Parms ':' '<IDENTIFIER>' ';' 'FORWARD' ';'
58 | -> FuncHead Parms ':' '<IDENTIFIER>' ';' Fblk Pblock ';';
59 |FuncHead -> 'FUNCTION' '<IDENTIFIER>';
60 |Parms ->
61 | -> '(' ParmList ')';
62 |ParmList -> ParmList ';' Parm
63 | -> Parm;
64 |Parm -> 'VAR' IdentList ':' SimpType
65 | -> IdentList ':' SimpType;
66 |Pblk -> ;
67 |Fblk -> ;
68 |
69 |StmtList -> StmtList ';' Stmt
70 | -> Stmt;
71 |Stmt -> 'IF' Boolean Then Stmt
72 | -> 'IF' Boolean Then Stmt Else Stmt
73 | -> 'WHILE' Boolean Do Stmt
74 | -> Repeat StmtList 'UNTIL' Boolean
75 | -> 'FOR' VarHead ':=' Boolean 'TO' Boolean Fup Stmt
76 | -> 'FOR' VarHead ':=' Boolean 'DOWNTO' Boolean Fdown Stmt
77 | -> Variable ':=' Boolean
78 | -> ProcCall
79 | -> '<IDENTIFIER>'
80 | -> 'GOTO' '<INTEGER>'
81 | -> Label ':' Stmt
82 | -> Block
83 | -> ReadWrite '(' IOList ')'
84 | -> ;
85 |Then -> 'THEN';
86 |Else -> 'ELSE';
87 |Fup -> 'DO';
88 |Fdown -> 'DO';
89 |Do -> 'DO';
90 |Repeat -> 'REPEAT';
91 |Label -> '<INTEGER>';
92 |ReadWrite -> 'READ'
93 | -> 'WRITE';
94 |
95 |IOList -> IOList ',' IOItem
96 | -> IOItem;
97 |IOItem -> Boolean
98 | -> '<string>';
99 |
100 |ProcCall -> '<IDENTIFIER>' '(' BoolList ')';
101 |BoolList -> BoolList ',' Boolean
102 | -> Boolean;
103 |
104 |Boolean -> BoolTerm
105 | -> Boolean 'OR' BoolTerm;
106 |BoolTerm -> BoolUnary
107 | -> BoolTerm 'AND' BoolUnary;
108 |BoolUnary -> BoolPri
109 | -> 'NOT' BoolPri;
110 |BoolPri -> Expr
111 | -> Expr Relop Expr;
112 |
MetaWare TWS Skeleton. 30-Sep-85 18:56:58 psg2.pg Page 3
LINE # |----+----1----+----2----+----3----+----4----+----5----+----6----+----7-
113 |Relop -> '<'
114 | -> '>'
115 | -> '<='
116 | -> '>='
117 | -> '='
118 | -> '<>';
119 |
120 |Expr -> Expr '+' Term
121 | -> Expr '-' Term
122 | -> Term;
123 |Term -> Term '*' Unary
124 | -> Term '/' Unary
125 | -> Term 'MOD' Unary
126 | -> Term 'DIV' Unary
127 | -> Unary;
128 |Unary -> Primary
129 | -> '-' Primary;
130 |Primary -> '(' Boolean ')'
131 | -> ProcCall
132 | -> Variable
133 | -> Constant;
134 |
135 |Variable -> VarHead VarExtension;
136 |VarHead -> '<IDENTIFIER>';
137 |VarExtension -> VarExtension VarExt
138 | -> ;
139 |VarExt -> '[' BoolList ']'
140 | -> '.' '<IDENTIFIER>';
141 |
142 |Constant -> '<REAL>'
143 | -> '<INTEGER>'
144 | -> 'TRUE'
145 | -> 'FALSE';
146 |ConstList -> ConstList ',' Constant
147 | -> Constant;
148 |Sint -> '<INTEGER>'
149 | -> '-' '<INTEGER>';
150 |end PSG
No user errors No warnings 286K of memory unused.
End of processing, 30-Sep-85 18:57:07 psg2.pg
MetaWare LALR(1) Grammar Analyzer. Today is 30-Sep-85 18:57:12
Removing the unit production for Pbegin
Removing the unit production for Var
Removing the unit production for SimpType
Removing the unit production for Then
Removing the unit production for Else
Removing the unit production for Do
Removing the unit production for Repeat
Removing the unit production for VarHead
Removing the unit production for Fup
Removing the unit production for Fdown
Removing the unit production for Label
Back substituting all productions for Program
Back substituting all productions for ProgHead
Back substituting all productions for ProgParms
Back substituting all productions for Block
Back substituting all productions for PFDecl
Back substituting all productions for ProcDecl
Back substituting all productions for FuncDecl
Back substituting all productions for Fblk
Back substituting all productions for VarExt
-- Grammar flattened (regular expressions removed).
Grammar: 60 terminals, 44 nonterminals, and 106 productions.
267 is the total right part length.
-- Grammar processing complete.
-- LR(0) parser: 247 states
454 terminal transitions
316 nonterminal transitions
217 nuclei items
-- Look-ahead sets:
Relation Examined/Edges SCCs Nodes
------------------------------------------
Reads 9/ 9 0 0
Follow 45/ 45 0 0
Includes 76/ 549 1 6
Lookback 21/ 560
38 final items in 38 states needed SLR(1) look-ahead sets.
3 final items in 2 states needed LALR(1) look-ahead sets.
39 look-ahead sets were used in total.
45 set unions for computing SLR(1) look-ahead sets.
111 set unions for computing LALR(1) look-ahead sets.
156 set unions total.
E : The grammar is NOT LALR(1). Here are the conflicts:
AFTER: 'PROGRAM' '<IDENTIFIER>' ';' Pblk LBList TYPList VRList ...
... PList 'BEGIN' 'IF' Boolean 'THEN' '<INTEGER>' ':' 'IF' Boolean ...
... 'THEN' Stmt state 217:
Read? 'ELSE'
Reduce? 44 Stmt -> 'IF' Boolean 'THEN' Stmt
{ 'ELSE' }
-- LALR(1) look-ahead conflict summary:
1 read /reduce conflicts in 1 states.
0 reduce/reduce conflicts in 0 states.
1 states with conflicts.
>>> Here are some traces for offending symbols in state 217 <<<<<<<<
PSG '<END_OF_FILE>'
'PROGRAM' '<IDENTIFIER>' ';' Pblk Pblock '.'
LBList TYPList VRList PList ...
... 'BEGIN' StmtList 'END'
Stmt
'IF' Boolean 'THEN' Stmt 'ELSE' Stmt
|
'<INTEGER>' ':' Stmt
'IF' Boolean ...
... 'THEN' Stmt
????? Reduce? 44 Stmt -> 'IF' Boolean 'THEN' Stmt
PSG '<END_OF_FILE>'
'PROGRAM' '<IDENTIFIER>' ';' Pblk Pblock '.'
LBList TYPList VRList PList ...
... 'BEGIN' StmtList 'END'
Stmt
'IF' Boolean 'THEN' Stmt
'<INTEGER>' ':' Stmt
'IF' Boolean ...
... 'THEN' Stmt . 'ELSE' Stmt
????? Read? 'ELSE'
>>> Here are the states with conflicts:
State 217, accessed by 'PROGRAM' '<IDENTIFIER>' ';' Pblk LBList ...
... TYPList VRList PList 'BEGIN' 'IF' Boolean 'THEN' Stmt
Terminal transitions Nonterminal transitions
'ELSE' -> 233
Look-ahead transitions
{ ';' 'ELSE' 'END' 'UNTIL' } -> 44 Stmt -> 'IF' Boolean 'THEN'
Stmt
The item set for this state is:
44 Stmt -> 'IF' Boolean 'THEN' Stmt .
233 | 45 Stmt -> 'IF' Boolean 'THEN' Stmt . 'ELSE' Stmt
>>> End of debugging information for LALR(1) look-ahead problems.
-- The grammar is NOT LALR(1) <<<<<<<<<<<<<<<<<<<<
-- Table packing:
1 multiply inconsistent states.
3 entries in the exception list.
241 nonterminal transitions saved by default.
454 terminal entries in the comb.
170 teeth in terminal portion.
166 are non-empty.
119 nonterminal entries in the comb.
319 teeth in entire comb.
285 are non-empty.
30 of 44 SLR(1) look-ahead sets were distinct.
Total (uncompressed) table size is
2238 bytes of parse tables
+ 768 bytes of vocabulary
+ 696 bytes of error recovery info
= 3702 total.
Parse tables written to disk.
1 user errors.
End of processing, 30-Sep-85 18:57:26
C:\TWS\TEST>